home *** CD-ROM | disk | FTP | other *** search
- opt pag,lis
- abs
- pag
- ttl "KISS - raw TNC handler"
-
- * KISS - a SLIP handler for the TAPR TNC1
- * Written by Marc Kaufman, WB6ECE
- * March 1987
- *
- * Modified by Gerard J Vandergrinten, PA0GRI.
- * Sept 1987
- * Copyright 1987 by Marc Kaufman, WB6ECE
- * All rights reserved
- *
- * Permission granted for noncommercial copying and use
- * provided this notice is retained.
-
- * Correction History:
- *
- * 4/17/87 - mtk: Initial Release (1.0)
- * 4/19/87 - mtk: Improve handling of timer values that are a
- * multiple of 65536 E-clock ticks
- * 4/30/87 - mtk: Correct error in format of TNC->Host block
- * by stuffing '0' before data
- * 8/10/87 - gjv: Make selfstart rom version,
- * Add FEND on start of frame,
- * Move initialized data to easy modifyable place.
- * 8/25/87 - gjv: Fix hdlc xmit state hfcs to complement
- * data to hdlc chip.
- * 12/14/87 - mtk: Receive block sometimes was prefixed by a garbage
- * byte. Don't start-stop the receiver, exept when
- * shifting into transmit mode.
- * 12/22/87 - gjv: Use second ram from tnc-1 if there. (more bufferring)
- * 12/22/87 - gjv: Fix command scanner for FESC sequences.
-
- * Refer to Phil Karn's description of KISS for details
- *
- * The following frame types (Host to TNC) are supported:
- *
- * 0 Data - data frame to HDLC channel
- * 1 TXDelay - 0 <= TXDelay <= 255 (* 10 ms.)
- * 2 Peristence - 255 -> transmit now
- * 3 SlotTime - 0 <= SlotTime <= 255 (* 10 ms.)
- * 4 TXTail - 0 <= TXTail <= 255 (* 10 ms.)
- * 5 HDX/FDX - 0 = HDX, 1 = FDX
- * 6 Speed - 0 < Speed <= 24 (slow TNC)
- * - 128+0 < Speed <= 128+48 (fast TNC)
- *
- * The Speed parameter sets the HDLC baud rate to (Speed*300) baud.
- * The high order bit (128), if set, indicates that the TNC1 is
- * running with a 2x clock. Maximum baud rates are 7200 for the slow
- * TNC, and 14400 for the fast TNC.
-
- * The following frame types (TNC to Host) are supported:
- *
- * 0 Data - data frame from HDLC channel
-
- * The normal idle state for the async receiver is "waiting for command"
- * after the trailing FEND from the previous packet.
-
- * Hardware addresses
-
- *** 6551 UART setup with speed from $f801
-
- acia equ $2010 base address
- acchar equ acia
- acstat equ acia+1
- accmnd equ acia+2
- acctrl equ acia+3
-
- as_fram equ $02 framing error only
- as_err equ $07 parity, framing, and overrun errors
- as_rdr equ $08 receive data register full
- as_xmt equ $10 xmit data register empty
- as_irq equ $80 acia interrupt request
-
- ac_dis equ $0a disable transmitter and receiver, set RTS
- ac_enb equ $09 enable receiver interrupts, set RTS
- ac_xmt equ $05 enable transmit and receive interrupts
-
- *** 6520 parallel i/o chip -- not used
-
- pia equ $2020 base address
- pra equ pia register A
- pcra equ pia+1 control A
- prb equ pia+2 register B
- pcrb equ pia+3 control B
-
- *** 6522 peripheral timer and i/o chip
-
- via equ $2040 base address
- vorb equ via output register B
- vora equ via+15 output register A, no handshake
- vddrb equ via+2 data direction register B
- vddra equ via+3 data direction register A
- vtim1cl equ via+4 low byte of timer 1 counter
- vtim1ch equ via+5 high byte of timer 1 counter
- vtim1ll equ via+6 low byte of timer 1 latch
- vtim1lh equ via+7 high byte of timer 1 latch
- vtim2l equ via+8 low byte of timer 2
- vtim2h equ via+9 high byte of timer 2
- vacr equ via+11 auxiliary control register
- vpcr equ via+12 peripheral control register
- vifr equ via+13 interrupt flag register
- vier equ via+14 interrupt enable register
-
- timrc1 equ vtim1cl both bytes of timer 1 counter
- timrl1 equ vtim1ll both bytes of timer 1 latch
- timer2 equ vtim2l both bytes of timer2 (counter and latch)
- v_int equ $20 timer2 interrupt bit (clear enable)
- vs_int equ $a0 timer2 interrupt bit (set enable)
- h_reset equ $ec reset HDLC chip (via vpcr)
- h_oper equ $ee operate HDLC chip (via vpcr)
- t_cntl equ $c0 timer1=free run, timer2=interval, sr=off
-
- *** WD 1933 HDLC chip equates
- *** IMPORTANT: this chip inverts Address and Data bits!!!
-
- hdlc equ $2800 base address
- hcr1 equ hdlc+7 control register 1
- hcr2 equ hdlc+6 control register 2
- hcr3 equ hdlc+5 control register 3
- hrhr equ hdlc+4 receive holding register
- hthr equ hdlc+3 transmit holding register
- hir equ hdlc+3 interrupt register
- hsr equ hdlc+2 status register
-
- fflags equ $01 cr2 - send flags between frames
-
- actrcv equ $80 activate receiver
- actran equ $40 activate transmitter
- actdtr equ $02 turn on DTR
- actptt equ $01 activate PTT line (misc. out)
-
- txon equ actran+actdtr+actptt preamble and data transmission
- rcvon equ actrcv+actdtr receiving
- h_data equ $00+txon Transmit commands
- h_abort equ $10+txon
- h_flag equ $20+txon
- h_fcs equ $30+txon (sends fcs + flag)
- h_MASK equ $cf
-
- reom equ $80 intreg - receive complete with no error
- reomerr equ $40 intreg - receive with error
- xcom equ $20 intreg - xmt command complete
- xcomerr equ $10 intreg - xmt error (underrun)
- dscchg equ $08 intreg - CD line state change
- drqi equ $04 intreg - input character available
- drqo equ $02 intreg - output character needed
- intrq equ $01 intreg - set if any of bits 3-7 are new
-
- CD equ $40 status - location of CD state bit
-
- ram0 equ $0000 bank 0 ram ($0000 - $1fff)
- ram0end equ ram0+8191 top of bank 0 ram
- ram1 equ $4000 bank 1 ram ($4000 - $5fff)
- ram1end equ ram1+8191 top of bank 1 ram
- rom equ $e000 top rom ($e000 - $ffff)
-
- FEND equ @300 frame end
- FESC equ @333 frame escape
- TFEND equ @334 transposed frame end
- TFESC equ @335 transposed frame escape
-
- CCZ equ $04 zero flag in CC
- CCNZ equ $fb non-zero flag in CC
- NOT equ $ff for negations
-
- stack equ $100 my stack is above debug stack
- org $100 local data starts at direct page 1
-
- *** Local Variables initialized from rom by startup code
-
- p_speed rmb 1 processor speed: 0= 1 Mhz, 1= 2 Mhz
- a_speed rmb 1 async speed
- h_speed rmb 1 (* 300) baud on hdlc
- u_txdly rmb 1 tx start delay (* 10 ms)
- u_pers rmb 1 persistence parameter
- u_slot rmb 1 slot time delay (* 10 ms)
- u_tail rmb 1 tx tail hold time (* 10 ms)
-
- c_txdly rmb 2 count value for txdelay
- c_slot rmb 2 count value for slot delay
- c_tail rmb 2 count value for tail delay
-
- cdval rmb 1 last CD status value (CD on)
- fxflag rmb 1 0 = hdx, 1 = fdx
- rand rmb 1 pseudo-random value (0 <= rand <= 255)
- savhc rmb 1 last hdlc command saved here
- svhir rmb 1 HDLC interrupt status saved here
- temp rmb 2
- tempih rmb 1 temp used by interrupt handler only
- upper_t rmb 1 upper 8 bits of 24 bit timer
- xmtok rmb 1 xmit flag: 0= rcv, +1= xmit ok, -1= xmit
- bdblk rmb 1 set if current block is "bad"
-
- * interrupt routine state information - initial values set
-
- ARCV rmb 2 acia receiver state
- AXMIT rmb 2 acia transmitter state
- HRCV rmb 2 hdlc receiver state
- HXMIT rmb 2 hdlc transmitter state
- TIMACT rmb 2 timer action state (after counted to zero)
-
- * i/o buffers
- *
- * this is a circular buffer system, with the buffer extending from
- * [FIRST] to [LIMIT-1]. IN is the real data in pointer. When the
- * block is accepted, AIN is updated to the value of IN.
-
- FIRST equ 0 pointer offsets for buffer header
- IN equ 2
- AIN equ 4 accepted data, IN pointer
- OUT equ 6
- LIMIT equ 8
-
- cmdsize equ 20 buffer for kiss control commands
- command rmb 10 cmdbuf,cmdbuf,cmdbuf,cmdbuf,cmdbuf+cmdsize
-
- * buffer from acia to hdlc
- abufh rmb 10 inbufend,inbufend,inbufend,inbufend,ram0end
-
- * buffer from hdlc to acia
- hbufa rmb 10 inbuffer,inbuffer,inbuffer,inbuffer,inbufend
-
- cmdbuf rmb cmdsize command buffer here, others at end of memory
- inbuffer rmb 2049
- inbufend equ *
- pag
- org $FFF2 Interrupt vector list
- *
- fdb jswi3
- fdb jswi2
- fdb jfirq
- fdb jirq
- fdb jswi
- fdb jnmi
- fdb main
- *
- org 0 Interrupt vector indirect area
- iswi3 rmb 2
- iswi2 rmb 2
- ifirq rmb 2
- iirq rmb 2
- iswi rmb 2
- inmi rmb 2
- *
-
- org $f800
-
- initv2 fcb 0 processor speed: 0= 1 Mhz, 1= 2 Mhz
- fcb 12 async port speed
- fcb 4 (* 300) baud on hdlc
- fcb 30 tx start delay (* 10 ms)
- fcb 64 persistence parameter (p=.25)
- fcb 10 slot time delay (* 10 ms)
- fcb 4 tx tail hold time (* 10 ms)
-
- fdb 0 count value for txdelay
- fdb 0 count value for slot delay
- fdb 0 count value for tail delay
-
- fcb CD last CD status value (CD on)
- fcb 0 0 = hdx, 1 = fdx
- fcb 0 pseudo-random value (0 <= rand <= 255)
- fcb 0 last hdlc command saved here
- fcb 0 HDLC interrupt status saved here
- fdb 0
- fcb 0 temp used by interrupt handler only
- fcb 0 upper 8 bits of 24 bit timer
- fcb 0 xmit flag: 0= rcv, +1= xmit ok, -1= xmit
- fcb 0 bad frame flag
-
- * interrupt routine state information - initial values set
-
- fdb await acia receiver state
- fdb asend acia transmitter state
- fdb hkillb hdlc receiver state
- fdb hsend hdlc transmitter state
- fdb 0 timer action state (after counted to zero)
-
- * i/o buffers
- *
- * this is a circular buffer system, with the buffer extending from
- * [FIRST] to [LIMIT-1]. IN is the real data in pointer. When the
- * block is accepted, AIN is updated to the value of IN.
-
-
- FDB cmdbuf,cmdbuf,cmdbuf,cmdbuf,cmdbuf+cmdsize
-
- * buffer from acia to hdlc
- FDB inbufend,inbufend,inbufend,inbufend,ram0end
-
- * buffer from hdlc to acia
- FDB inbuffer,inbuffer,inbuffer,inbuffer,inbufend
- inite2 equ *
- initl2 equ inite2-initv2
-
- * next are buffer pointers if extra ram is installed.
- initv3 equ *
- * buffer from acia to hdlc
- FDB inbuffer,inbuffer,inbuffer,inbuffer,ram0end
-
- * buffer from hdlc to acia
- FDB ram1,ram1,ram1,ram1,ram1end
- inite3 equ *
- initl3 equ inite3-initv3
-
- * interrupt re-vector area: parallel to fff0-ffff
-
- jswi3 jmp [iswi3]
- jswi2 jmp [iswi2]
- jfirq jmp [ifirq]
- jirq jmp [iirq]
- jswi jmp [iswi]
- jnmi jmp [inmi]
- *
- * Initialize values for low core.
- * They MUST match the values they replace..
- *
- initv1 fdb main 0000
- fdb main 0002
- fdb main 0004
- fdb action 0006
- fdb main 0008
- fdb main 000A - last vector used
- inite1 equ *
- initl1 equ inite1-initv1
-
- *** Main program
- *
- * First copy a default parameter block to ram.
- * Next setup our devices.
- * Finaly start playing and KISS.
- *
-
- setdp $01
- main orcc #$50 turn off interrupts (FIRQ + IRQ)
- lda #1
- tfr A,DP set base page register to our variables
- lds #stack set stack to our local stack
-
- *
- * move default values to low core !?????
- *
- ldx #$0000 desitination
- ldy #initv1
- ldb #initl1
- l_ini1 lda 0,y+
- sta 0,x+
- dec b
- bne l_ini1
- *
- ldx #$0100
- ldy #initv2
- ldb #initl2
- l_ini2 lda 0,y+
- sta 0,x+
- dec b
- bne l_ini2
-
- *
- * test if extra ram is available
- *
- ldd #$aa55
- std ram1
- lda ram1
- cmp a #$aa
- bne main1 not there
- lda ram1+1
- cmp a #$55
- bne main1 faultly memory..
-
- * move large buffer pointers to low core
-
- ldx #abufh
- ldy #initv3
- ldb #initl3
- l_ini3 lda 0,y+
- sta 0,x+
- dec b
- bne l_ini3
-
- * reset and disable UART
- main1 lda a_speed initialize from preset data
- sta acstat reset device
- ora #$10 8 bit word, 1 stop, intern clock
- sta acctrl
- lda #ac_dis turn off receiver, set RTS only
- sta accmnd
-
- * reset 6520 Not used by this program
- clra
- sta pcra disable pia-A
- sta pcrb disable pia-B
-
- * reset 6522 NOVROM is not used, only timers are used
- lda #h_reset
- sta vpcr clear CA2 to reset HDLC chip
- lda #t_cntl
- sta vacr reset 6522 timer and shift register
- lda #$f0
- sta vora set A output bits to '1'
- sta vddra turning off NOVROM access
- lda #$bf
- sta vorb set B output bits to '1'
- sta vddrb driving NOVROM address to all 1's
- lda #$7f
- sta vier disable all 6522 interrupts
- sta vifr clear all 6522 interrupts
- lda #h_oper clear HDLC reset bit, operate mode
- sta vpcr reset 6522 control modes (CB2=1, CA2=1)
-
- pag
- *
- * preset
- jsr setdelay compute delay counter values
- lda #CD pretend CD set upon entry
- sta cdval
-
- * setup hdlc chip
- * first, wait for at least 2.5 TC cycles...
- ldb #3*32 2.5 to 3 cycles
- pw_0 lda vorb
- bmi pw_0 wait for 0
- pw_1 lda vorb
- bpl pw_1 wait for 1 (1/2 cycle)
- decb
- bne pw_0
-
- clra
- sta savhc
- coma
- sta hcr3 no transmit residue
- sta hcr2 8-bit characters, no address comp
- **
- lda #ac_xmt turn on acia, set RTS
- sta accmnd
-
- lda #FEND Send a first byte out
- sta acchar to start this ballgame
-
- pw_2 lda #rcvon start hdlc receiver
- tst fxflag
- beq hdon half duplex
- ldb #fflags turn on auto-flag
- comb
- stb hcr2
- ldx #hfdxs
- stx HXMIT state to begin full duplex ops
- ldb #1
- stb xmtok transmit is always ok
- ora #actptt activate ptt
- hdon sta savhc
- coma
- sta hcr1
-
- jsr hdsc check current CD state
-
- cli TURN ON INTERRUPTS
- pag
- *** Main loop, non-interrupt mode
-
- loop ldy #command look for commands
- jsr getbuf
- bne lpax no command
- tab
- cmpa #FESC
- bne lp_b Not an escaped char
- jsr getbuf get escaped char
- cmpa #TFEND is a FEND escaped ?
- bne lp_a
- ldb #FEND
- bra lp_b
- lp_a cmpa #TFESC
- bne lp_b escape sequence error leave b as is.
- ldb #FESC
-
- lp_b jsr getbuf get second command byte
- cmpa #FESC
- bne lp_d Not an escaped char
- jsr getbuf get escaped char
- cmpa #TFEND is a FEND escaped ?
- bne lp_c
- lda #FEND
- bra lp_d
- lp_c cmpa #TFESC
- bne lp_d escape sequence error leave b as is.
- lda #FESC
- lp_d sta temp
- jsr getbuf must be FEND
- cmpa #FEND
- bne badcmd bad command, kill it
- lda temp
-
- lp_1 decb tx delay
- bne lp_2
- sta u_txdly
- bra recomp recompute delays
-
- lp_2 decb persistence
- bne lp_3
- sta u_pers
- bra lpax
-
- lp_3 decb slot time
- bne lp_4
- sta u_slot
- bra recomp
-
- lp_4 decb tx tail
- bne lp_5
- sta u_tail
- bra recomp
-
- lp_5 decb hdx/fdx
- bne lp_6
- cmpa fxflag is this a change?
- beq lp_6 no
- sta fxflag
- jmp pw_2 jump to full / half check.
-
- lp_6 decb baud rate and processor speed
- bne lpax ..unrecognized
- anda #$7f baud rate
- sta h_speed
- lda temp
- anda #$80 for TNC1 - fast processor flag
- sta p_speed
- recomp jsr setdelay recompute delays and baud rate
- bra lpax
-
- badcmd jsr getbuf purge command buffer
- bne lpax buffer empty
- cmpa #FEND
- bne badcmd
-
- * if the acia is idle, but with interrupts enabled, the TXempty bit is 0
- * so we can't check that...
- lpax lda accmnd is acia transmitter running
- cmpa #ac_xmt
- beq lpah yes
- ldy #hbufa is there data to send
- ldx AIN,Y
- cpx OUT,Y
- beq lpah no
- **
- sei turn off interrupts
- lda accmnd
- cmpa #ac_xmt
- beq lpac cant start if acia running
- jsr [AXMIT] start the acia transmitter
- lpac cli turn on interrupts
- **
-
- * check for transmit data to HDLC line in a similar fashion
- lpah tst xmtok OK to go?
- ble lplp no
- ldy #abufh
- ldx AIN,Y is there data to send
- cpx OUT,Y
- beq lplp no
- **
- sei repeat test with interrupts off
- tst xmtok
- ble lpnh
- ldy #abufh
- ldx AIN,Y
- cpx OUT,Y
- beq lpnh
- jsr [HXMIT] start the hdlc transmit process
- lpnh cli turn interrupts back on
- **
-
- lplp jmp loop
- pag
-
- *** Interrupt Handler - main code
-
- action lda acstat first check for acia activity
- bpl chkh none, check hdlc
- bita #as_rdr is there any receive data
- beq chkax no, check transmit
-
- jsr [ARCV] acia receive action
- lda acstat
- bpl chkh no transmit action
-
- chkax bita #as_xmt is transmitter empty
- beq chkh no
-
- jsr [AXMIT] acia transmitter action
-
- chkh lda hir HDLC interrupt register
- coma
- bita #intrq
- bne chkh_1 upper bits are significant
- anda #drqo+drqi only data bits are significant
- beq cktim nothing, check timer
- chkh_1 sta svhir save it, since chip is now reset
- bita #drqi+reom+reomerr is there receiver status
- beq chkhx no receive action
-
- jsr [HRCV] perform receiver action
- lda svhir
-
- chkhx bita #drqo+xcom+xcomerr is there transmitter status
- beq chkhs no transmitter action
-
- jsr [HXMIT] perform transmitter action
- lda svhir
-
- chkhs bita #dscchg data set change
- beq cktim none, check timer
-
- jsr hdsc perform data set change action
-
- cktim lda vifr 6522 interrupt flag register
- bpl xint no timer interrupt
-
- jsr dotime handle timer
-
- xint rti exit interrupt main loop
- pag
-
- *** Interrupt Action Routines
-
- *** ACIA receiver actions
-
- gowait ldy #ARCV
- jsr xstate
-
- await equ * State - wait for FEND
- ldb acchar read character
- bita #as_err check for receiver errors
- bne cstate yes, continue waiting (same state)
- cmpb #FEND is this the start of a frame
- bne cstate no, continue waiting (same state)
-
- agetcom ldy #ARCV get block type byte
- jsr xstate step state
- ldb acchar read command character
- bita #as_err check for receiver errors
- bne gowait yes, resync on FEND
- tstb is command 00
- beq agetdat yes, get data
- dea nop
- cmpb #FEND extra FEND?
- beq cstate yes, ignore it (stay in this state)
- tba
- ldy #command
- jsr putbuf
- bne gowait putbuf failed, ignore command, sorry!
-
- abldcmd ldy #ARCV build command
- jsr xstate
- ldy #command command buffer area
- bra abuild
-
- cstate rts stay in current state
-
- agetdat ldy #ARCV get data
- jsr xstate
- ldy #abufh data buffer area
-
- abuild ldb acchar read next byte
- bita #as_err check for receiver errors
- bne adumpc yes, dump data gathered so far
- tba
- jsr putbuf add byte to buffer
- bne adumpc putbuf failed, dump data
- cmpa #FEND last byte?
- bne cstate no, continue to gather data
- ldx IN,Y accept data
- stx AIN,Y
- bra agetcom next byte should be command again
-
- adumpc ldx AIN,Y dump accumulation of data
- stx IN,Y
- cmpa #FEND was failure on last byte
- bne gowait no, wait for FEND
- bra agetcom yes, get command again
- pag
-
-
- *** ACIA transmitter actions
-
- axsend ldy #AXMIT
- jsr xstate
- asend equ * Transmitter active on entry
- ldy #hbufa
- jsr getbuf get next character to send to host
- bne axnone none, turn off transmit
- sta acchar send the char
- rts stay in this state
-
- axnone lda #ac_enb turn off transmit interrupts
- sta accmnd
- ldy #AXMIT
- jsr xstate
-
- ldy #hbufa attempt to restart transmitter
- jsr getbuf
- bne cstate no character, dont start
- ldb #ac_xmt re-enable interrupt
- stb accmnd
- sta acchar send the character
- bra axsend flip to other state
- pag
-
-
- *** HDLC receive actions
-
- hkillb ldy #hbufa kill receive block
- ldx AIN,Y
- stx IN,Y
- *
- * initialize the header for KISS frame
- *
- gohrec lda #FEND Frame delimiter first
- jsr putbuf
- clra next byte indicates DATA block
- sta bdblk clear bad block flag
- jsr hputbuf
-
- ldy #HRCV
- jsr xstate
-
- hrec equ * receive characters here
- bita #drqi do we have a character
- beq hrckend no, check end cases
- ldy #hbufa receive buffer
- lda hrhr receive character
- coma
- cmpa #FEND check special cases
- beq hrec_1
- cmpa #FESC
- bne hrec_2 ordinary character
- ldb #TFESC
- bra hrec_1a
- hrec_1 ldb #TFEND
- hrec_1a lda #FESC
- jsr hputbuf put character in buffer
- tba
- hrec_2 jsr hputbuf put character in buffer
- lda svhir
- bita #reom was this also end of message
- bne hreom
- bita #reomerr was this also an error end
- bne hkillb
- rts continue (stay in this state)
-
- hrckend bita #reom normal end
- beq hkillb no, kill receive block
-
- * The WD chip has read in the bcc before giving us the eom indication.
- * We must back over it
-
- hreom ldy #hbufa
- jsr back2 back up 2 characters
- bne hkillb (system) error in backing
- lda #FEND
- jsr hputbuf
- tst bdblk check for a valide frame (no errors)
- bne hkillb buffer full
- ldx IN,Y accept data
- stx AIN,Y
- bra gohrec set to receive next block
- pag
-
-
- *** HDLC transmit actions
-
- gohsend ldy #HXMIT
- jsr xstate
-
- hsend equ * initial transmit state
- lda #-1 signal transmit active
- sta xmtok
- tst fxflag is this full duplex
- bne hstart yes, start sending immediately
- lda savhc
- anda #NOT-actrcv turn off receiver if half duplex
- sta savhc
- lda #2
- sta bdblk abort any partial block received
- ldx c_txdly pre-xmit delay
- beq hstart no delay
- clra pre-start, send zeros for sync
- coma (this gives faster DPLL lockup)
- sta hthr
- lda #h_data send data
- jsr setcr1
- ldd c_txdly start timer
- ldx #hset1
- jsr settime
-
- ldy #HXMIT pre-start state, just send more zeros
- jsr xstate
- bita #drqo check for normal entry
- lbeq hxabt abort, abnormal termination
- clra
- coma
- sta hthr send another zero
- rts stay in this state until timer runs out
-
- **
- hset1 ldx #hstart Timer action: start block
- stx HXMIT
- rts
- **
-
- hstart ldy #abufh
- jsr getbuf get first character of frame
- coma
- sta hthr this prevents DRQO interrupts...
- tst fxflag is this full duplex
- bne hsdat yes, can go immediately
- lda #h_flag if half duplex, send leading flag
- bra hsgo
-
- hfdxs lda #-1 initial full duplex start
- sta xmtok
- lda savhc
- ora #actran turn on transmitter..
- sta savhc
- coma
- sta hcr1
- bra hsendc wait for DRQO and start
-
- hendf lda #h_fcs send fcs + done
- bra hxab_E
-
- hfcs jsr getbuf is there another frame
- bne hendf no
- cmpa #FEND is this a null frame
- beq hfcs yes, skip it
- coma
- sta hthr load first character of next frame..
- lda #h_fcs
-
- hsgo jsr setcr1 send flag or fcs before frame
-
- ldy #HXMIT
- jsr xstate set next state
-
- bita #xcom
- beq hxabt abort on error
- hsdat lda #h_data put us into data mode for frame
- jsr setcr1 (first character goes now...)
-
- ldy #HXMIT
- jsr xstate
-
- hscont ldy #abufh
- jsr getbuf get next character
- bne hxab_H out of data, without FEND (internal error)
- cmpa #FESC escape
- bne hsenda ordinary character
- jsr getbuf get character following FESC
- tab
- lda #FEND
- cmpb #TFEND
- beq hsendb
- lda #FESC these are all of the cases (today)
- cmpb #TFESC
- beq hsendb
- tba recover character, invalid escape
- hsenda cmpa #FEND
- beq hfcs done, send fcs
- hsendb coma
- sta hthr send character
-
- hsendc ldy #HXMIT
- jsr xstate set next state
-
- bita #xcomerr error sending
- beq hscont continue if no error
-
- hxabt ldy #abufh error sending, scrap entire message
- hxab_1 jsr getbuf
- bne hxab_H
- cmpa #FEND
- bne hxab_1
- hxab_H lda #h_abort
-
- hxab_E jsr setcr1 send the abort or fcs at end
-
- ldy #HXMIT
- jsr xstate
-
- ldd c_tail post-xmit timer
- beq hxdone no waiting
- ldx #hxdone
- jsr settime start tail timer
- ldy #HXMIT
- jsr xstate
-
- clra
- coma
- sta hthr make DRQO interrupts go away
- rts return - no interrupts until timer done
-
- hxdone lda #1 not transmitting
- sta xmtok
- tst fxflag full duplex?
- bne hxd_1 yes, don't turn off ptt
-
- lda savhc
- anda #NOT-actran-actptt turn off transmitter
- ora #actrcv turn on receiver
- sta savhc
- coma
- sta hcr1
- clr xmtok receiving flag
- lda #CD
- sta cdval re-examine CD state
- bsr hdsc
-
- hxd_1 jmp gohsend return to starting state
- pag
-
-
- *** Carrier-sense change handler
-
- hdsc lda hsr read status register
- tst fxflag are we full duplex?
- bne hdrts yes, no action needed
- coma
- anda #CD look at CD bit
- cmpa cdval compare with saved value
- beq hdrts same, no action
- sta cdval save new value
- beq hdsoff now off
-
- hdson tst xmtok hdx - are we transmitting now?
- bmi hdrts yes, will turn on at end of xmit
- clr xmtok set state to receiving
- lda #v_int
- sta vier disable timer2 interrupt, if active
- ldd timer2
- hdrts rts return
-
- hdsoff tst xmtok are we transmiting?
- bne hdrts yes, if half duplex this is false indication
- bra pwait always wait 1 slot time at least...
-
- persist jsr getran get a random number
- cmpb u_pers compare against persistence value
- bls setxok ok to transmit
- pwait ldd c_slot no, wait 'slot' time and retry
- ldx #persist
- bra settime start timer
-
- setxok lda #1 ok to transmit now
- sta xmtok
- rts
- pag
-
-
- *** Timer handling
-
- dotime ldd timer2 clear timer interrupt and read timer
- tst upper_t
- beq tdone timer expired
- dec upper_t
- tsta
- bne dot_1 correct for nn00 to (nn-1)ff
- incb
- dot_1 std timer2 reenable interrupt
- rts done with timer
-
- tdone lda #v_int timer2 interrupt bit
- sta vier disable interrupt
- lda timer2
- jmp [TIMACT] do timer action
- pag
-
-
- *** Interrupt Support Subroutines
-
- * SETCR1 - set type of transmit in hcr1 - done often
- *
- * entry: A = new data/flag/abort type to set
- setcr1 sta tempih
- lda savhc
- anda #h_MASK
- ora tempih
- sta savhc
- coma
- sta hcr1
- rts
-
- * SETTIME - start timer with specified action
- *
- * entry: D = upper 16 bits of 24 bit timer value
- * X = location of timer action routine
- *
- settime stx TIMACT store action address
- sta upper_t upper 8 bit of timer value
- clra
- tstb is timer value 0 mod 65536
- bne sett_1 no
- dec upper_t yes, tick over one count
- bmi tdone all zero count, finish immediately
- coma
- comb set D = $ffff
- sett_1 std timer2 start timer with residual mod 65536
- lda #vs_int enable timer2 interrupt
- sta vier
- rts
-
- * XSTATE - set new state for interrupt task
- *
- * entry: address of state jump word in Y
- *
- xstate puls X get return address into X
- stx 0,Y save it as state address
- rts return to state caller
- pag
-
-
- *** General Subroutines
-
- * GETBUF, PUTBUF - handle getting or putting characters from/to buffers
- *
- * entry: buffer head address in Y
- * exit: zero flag set if all is well, NZ otherwise (overflow or empty)
- *
- getbuf ldx OUT,Y get the OUT pointer
- cpx AIN,Y check for data present
- beq nobuf no data, set NZ and exit
- lda 0,X get the data
- bsr incbuf increment pointer value
- stx OUT,Y new pointer
- yesbuf orcc #CCZ set Z flag
- rts
-
- putbuf ldx IN,Y get the IN pointer
- tfr X,U save it in a convenient place
- bsr incbuf next value of IN
- cpx OUT,Y is the buffer full
- beq nobuf yes, operation fails
- sta 0,U no, store the data
- stx IN,Y new pointer
- bra yesbuf
-
- nobuf andcc #CCNZ clear Z flag
- rts
-
- incbuf inx increment pointer
- cpx LIMIT,Y at limit
- bne incrts no
- ldx FIRST,Y yes, wrap to first
- incrts rts
-
- *
- * HPUTBUF - like putbuf, but sets bdblk if put failed
- *
- hputbuf bsr putbuf go put in buffer
- beq hputrts OK just return
- lda #1 abort frame flag
- sta bdblk
- hputrts rts
-
- * BACK2 - back up in buffer -- used to back up over bcc received
- *
- * entry: buffer head address in Y
- *
- * A good block should leave at least 2 data characters plus the bcc
- * in the buffer. The backup algorithm takes advantage of this
- * when over-backing to check for FESC
- *
-
- back2 ldx IN,Y
- cpx AIN,Y
- beq nobuf whoops.. shouldn't happen (system error)
- bsr back1
- bne incrts error
- bsr back1
- bne incrts error
- stx IN,Y
- bra yesbuf no error
-
- back1 bsr decbuf back up
- bne incrts hit old AIN
- bsr decbuf
- bne incrts
- lda 0,X
- cmpa #FESC
- beq yesbuf 2 back was FESC, so 1 back was escaped
- bsr incbuf 1 back was good
- bra yesbuf
-
- decbuf cpx FIRST,Y
- bne decb_1
- ldx LIMIT,Y
- decb_1 dex
- cpx AIN,Y
- bne yesbuf ok, not at AIN
- bra nobuf whoops.. shouldn't happen (system error)
-
- * GETRAN - get a random number in B
- *
- * uses mixed congruential generator: X' = 21*X + 53
- *
- getran lda #21
- ldb rand previous value
- mul
- addb #53
- stb rand
- rts
-
- * SETDELAY - compute delay values and set baud rate counter
- *
- setdelay ldb #36 = 921600 / 256 (* .01 seconds)
- tst p_speed is this a fast processor/counter
- beq _setd1 no
- aslb yes, double the count required
- _setd1 stb temp
- lda u_txdly units of tx delay
- mul
- std c_txdly
- ldb temp
- lda u_slot units of slot delay
- mul
- std c_slot
- ldb temp
- lda u_tail units of tx tail delay
- mul
- std c_tail
-
- tst h_speed speed requested for hdlc
- bne _seth1 legal speed requested
- lda #4 default to 1200 on error
- sta h_speed
- _seth1 ldb #96 = 300 baud at fast processor clock
- clra
- _seth2 inca
- subb h_speed
- bgt _seth2 divide 96 by multiple of 300 baud desired
- tst p_speed now check processor speed
- bne _seth3 fast
- lsra slow, divide result by 2
- _seth3 suba #2 counter always takes 2 more per half cycle
- bmi _seth4 too fast, ignore request
- clrb
- std timrc1 store baud rate in timer 1 COUNTER to start it
- _seth4 rts
-
-
- fcc 'TNC-1 KISS firmware WB6ECE, PA0GRI 22 dec 1987'
-
- end
-
-